perm filename RECUR.PUB[2,TES] blob sn#038071 filedate 1973-04-25 generic text, type T, neo UTF8
00050	.TURN ON "#∪↓_" 
00100	.PAGE FRAME 61 HIGH 80 WIDE;
00150	.TEXT AREA TEXT LINES 1 TO 60 CHARS 1 TO 80;
00200	.TITLE AREA FOOTING LINE 61;
00250	.PLACE TEXT;
00300	.COUNT PAGE FROM 1 TO 999; EVERY FOOTING(,{PAGE},);
00350	.MACRO ASIS ⊂ BEGIN NOJUST NOFILL ⊃
00400	.MACRO FIG(N) ⊂ SKIP N ⊃
00450	.MACRO SK(N) ⊂ SKIP N ⊃
00500	.BEGIN FILL ADJUST INDENT 0,0
00550	.ASIS
00600	                         ↓_RECURSION_↓
00650	.END
00700	.SK 4
00750	These notes introduce a programming technique called
00800	↓_recursion_↓.  This technique does not require any new
00850	ALGOL W commands, but rather uses the facilities we have
00900	already introduced, particularly procedures, in a new way.
00950	We shall illustrate the recursion technique with
01000	a number of examples; these range from cases where recursion
01050	seems a needlessly difficult method of solving the problem
01100	to cases where it is a very natural method.
01150	
01200	↓_Example 1: Counting Marbles_↓
01250	
01300	Suppose you have two bags full of marbles:
01350	a red bag full of red marbles and a green bag full of
01400	green marbles.  You wish to answer the question: are there (a)
01450	more red marbles than green marbles, (b) more greens than reds,
01500	or (c) equal numbers of marbles.
01550	
01600	↓_Method 1.0:_↓ The simplest technique would be to count the number
01650	of red marbles (say R) and the number of green marbles (say G),
01700	Then our answers are:
01750	.ASIS
01800	
01850		(a) if R > G
01900		(b) if G > R
01950		(c) if G = R
02000	
02050	.END
02100	However, this method is very inefficient in certain cases.
02150	Suppose we counted and found R = 10 and G = 150000.
02200	Clearly, we have expended a lot of effort in counting the green
02250	marbles, although the effort required to answer the
02300	question is much less.
02350	
02400	↓_Method 1.1:_↓ To avoid the inefficiency, we could proceed
02450	as follows:
02500	.SK 1
02550	.BEGIN INDENT 6,3
02600	1.#If the red bad and green bag are both empty, announce
02650	that the answer is (c).  If not, go to step 2.
02700	
02750	2.#If the red bag is empty, then the answer is (b). Otherwise
02800	proceed:
02850	
02900	3.#If the green bag is empty, then the answer is (a).  Otherwise,
02950	go to step 4.
03000	
03050	4.#If we come to this step, neither bag is empty.  Remove
03100	one marble from the red bag and one from the
03150	green bag.  Then go to step 1.
03200	.END
03250	.SK 1
03300	This procedure only "counts" (step 4) enough marbles to solve
03350	the problem.  Furthermore, notice that we never really process
03400	↓_numerical_↓ quantities R or G; thus the technique
03450	can be extended to non-numerical processes (**** comparing strings?).
03500	
03550	We can express steps 1 to 4 in an ALGOL W notation as follows:
03600	.ASIS
03650	
03700	WHILE green_bag_not_empty AND red_bag_not_empty DO
03750	    BEGIN
03800	    remove_marble_from_red_bag;
03850	    remove_marble_from_green_bag
03900	    END;
03950	IF green_bag_not_empty THEN answer_is_b ELSE
04000	IF red_bag_not_empty THEN answer_is_a ELSE
04050	                              answer_is_c ;
04100	
04150	.END
04200	(Note: the expressions in lower case above are not legal
04250	ALGOL W constructs; they merely suggest what must be filled
04300	in.)  This method is called an "iterative solution" because
04350	an indefinite iterative loop is used to construct the program.
04400	
04450	↓_Method 1.2:_↓ This problem can also be solved with the recursion
04500	technique.  We shall initially illustrate the method
04550	with a rather inane "story."  Suppose that Tom is the owner of the
04600	bags and has an inexhaustible supply of friends (Huck, Becky, etc.).
04650	We shall simplify our notation for Tom and friends
04700	to PERSON0 (Tom), PERSON1, PERSON2, etc.  Tom's last name is
04750	(predictably) Sawyer, and he conceives an ingenious plan for
04800	answering the bags question without his doing any work.
04850	He will give each friend the following instructions:
04900	.SK 1
04950	.BEGIN INDENT 6,3
05000	1.#When you are handed two bags by someone, inspect them carefully
05050	and perform the following steps.
05100	
05150	2.#If both bags are empty, tell the person who handed the bags
05200	to you that the answer is "c".  Then you are finished, and can go
05250	to the picnic, get lost in the cave, etc.
05300	
05350	3.#If the red bag is empty, tell the person who handed
05400	it to you that the answer is "b" and go play.
05450	
05500	4.#If the green bag is empty, tell the person who
05550	handed it to you that the answer is "a" and go play.
05600	
05650	5.#If steps 2-4 didn't apply, you can't go play quite yet.
05700	Remove one marble from each bag.  Then find a free (as yet unused)
05750	person and give both bags to him/her.  Now wait until that
05800	person tells you the "answer" (this will certainly happen).
05850	Then repeat this answer to the person who originally handed the
05900	bags to you.  Now go play.
05950	.END
06000	.SK 1
06050	Tom (PERSON0) starts the process by giving the bags to PERSON1.
06100	If necessary, he/she passes them to PERSON2 in the course of
06150	executing the above instructions, etc.
06200	
06250	Let us show diagramatically the process for G = 4, R = 3.
06300	
06350	.SK 2
06400	.BEGIN INDENT 30,30
06450	Tom (PERSON0) hands the bags to PERSON1 and waits for an answer.
06500	PERSON1 discovers that none of steps 2-4 apply, and removes a marble
06550	frommeach bag (step 5) and hands them to PERSON2.
06600	.SK 3
06650	PERSON2 likewise discovers that steps 2-4 aren't true, removes a
06700	marble from each bag, and hands off to PERSON3, and awaits PERSON3's
06750	answer.
06800	.SK 3
06850	And to PERSON4.
06900	.SK 4
06950	Now PERSON4 discovers that the red bag is empty, so
07000	he/she is instructed to tell PERSON3 that the answer is "b" and
07050	then go ply (step 3).
07100	.SK 4
07150	Then PERSON3 is instructed (by step 5) to repeat the answer to
07200	PERSON2 and go play.
07250	.SK 4
07300	and so forth until PERSON1 tells our hero that the
07350	answer is "b".
07400	.SK 4
07450	.END
07500	This process has consumed quite a quantity
07550	of resources (friends) and has seemed needlessly complicated.
07600	It might have been more natural for Tom to sit down with his
07650	bags and use method 1.1 to arrive at an answer.  However, we
07700	shall see below that some problems are ↓_easier_↓ to formulate
07750	with recursion (method 1.2) than iteration (method 1.1).
07800	
07850	We shall not carry this example furhter, or try to write an
07900	ALGOL W program that mimics the recursive solution of this ppoblem.
07950	However, we shall make the following characterization of a
08000	recursive solution:
08050	.SK 1
08100	.BEGIN INDENT 6,3
08150	1.#Apply some tests to see if the problem is so trivial that
08200	it can be solved directly.  Steps 2-4 of the example are such tests.
08250	
08300	2.#If the solution is not trivial, express the solution of the
08350	problem in terms of the solution of a slightly simpler problem
08400	(e.g. the problem of answering the question for bags with
08450	one fewer marble in each one).  Then find a new PERSON to solve the
08500	slightly simpler problem.  When he/she returns an answer,
08550	you can then formulate the answer to the original problem
08600	(in the example above, the answer to the original problem is
08650	the same as the answer to the simpler problem -- hence we
08700	merely repeat the answer).
08750	.SK 2
08800	.END
08850	↓_Example 2: The Factorial Function_↓
08900	
08950	We shall now illustrate the iterative and recursive formulations
09000	of a specific computational problem: computing the factorial
09050	of a number.  We can express the factorial of a number, n, as follows:
09100	.ASIS
09150	
09200		factorial(n) = n * (n-1) * (n-2) * ... * 2 * 1
09250		factorial(0) = 1
09300	
09350	.END
09400	Notice that factorial is not defined for n < 0.  This formulation
09450	immediately suggests an iterative solution.
09500	
09550	↓_Method 2.1:_↓ Iterative Solution to Factorial
09600	
09650	The special case of factorial(0) can be removed by rewriting
09700	the definition slightly (multiplying any expression by 1 leaves
09750	its value unchanged):
09800	.ASIS
09850	
09900		factorial(n) = 1 * 1 * 2 * ... * (n-2) * (n-1) * n
09950	
10000					   n terms in all
10050	
10100	.END
10150	Thus, for n = 0, we have zero terms following the initial
10200	"1", and factorial(0) = 1.  Here is an ALGOL W procedure that
10250	computes factorial:
10300	.ASIS
10350	
10400	INTEGER PROCEDURE FACTORIAL (INTEGER VALUE N);
10450	BEGIN INTEGER M;
10500	   M := 1;
10550	   FOR I := 1 UNTIL N DO
10600	      M := M * I ;
10650	   M
10700	END;
10750	
10800	.END
10850	You may wish to "hand compute" several values of factorial
10900	using this technique to see that it is correct.
10950	A brief table of factorials is:
11000	.ASIS
11050	
11100		n		factorial(n)
11150		0		   1
11200		1		   1
11250		2		   2
11300		3		   6
11350		4		  24
11400		5		 120
11450		6		 720
11500	
11550	.END
11600	.SK 2
11650	↓_Method 2.2:_↓ Recursive Solution to Factorial
11700	
11750	Let us try to formulate the factorial problem in the recursive
11800	paradigm described above:
11850	.SK 1
11900	.BEGIN INDENT 6,3
11950	1.#If the problem is trivially solvable, compute the answer.
12000	
12050	2.#Otherwise, use the same procedure to answer a
12100	simpler problem, and then compute the answer to the original
12150	problem based on this answer.
12200	.SK 1
12250	.END
12300	Writing the definition of factorial again:
12350	.ASIS
12400	
12450		factorial(n) = n * (n-1) * (n-2) * ... * 2 * 1
12500	
12550	.END
12600	We see that the epxression on the right can be broken into two parts:
12650	n (the first term) and all remaining terms:
12700	.ASIS
12750	
12800		factorial(n) = [n] * [(n-1)*(n-2)* ... *2*1]
12850	
12900	.END
12950	The second quantity inside square brackets is just exactly
13000	the expression for factorial(n-1), which we obtain by substituting
13050	n-1 for n in the original definition:
13100	.ASIS
13150	
13200		factorial(n-1) = (n-1) * (n-2) * (n-3 ) * ... * 2 * 1
13250	
13300	.END
13350	Hence we have:
13400	.ASIS
13450	
13500		factorial(n) = n * factorial(n-1)
13550	
13600	.END
13650	Buth this is not quite correct for our special case of n = 0.
13700	We know that factorial(0) = 1, but the above definition would have
13750	it be
13800	.ASIS
13850	
13900		factorial(0) = 0 * factorial(-1)
13950	
14000	.END
14050	which is probably not 1 (remember that factorial is not
14100	even defined for negative numbers!).  So we must alter our definition
14150	to include the special case:
14200	.ASIS
14250	
14300		factorial(n) ↓_is_↓
14350		   if n=0 then the answer is 1
14400		   otherwise the answer is n * factorial(n-1)
14450	
14500	.END
14550	This definition now matches exactly the recursive
14600	paradigm!  The "trivial problem" that we know the answer to
14650	is factorial(0).  In all other cases, if we can compute
14700	the answer to a slightly simpler problem (factorial(n-1))
14750	we can compute the answer to the original problem (factorial(n)).
14800	
14850	We can not compose the instructions for our stick-figure
14900	computing persons:
14950	.SK 1
15000	.BEGIN INDENT 6,3
15050	1.#If you are asked to compute the factorial of a number, say n,
15100	do he following steps:
15150	
15200	2.#If n is zero, tell the person who asked you to compute factorial
15250	that the answer is "1"; then go play.
15300	
15350	3.#Otherwise, find an unoccupied person, and ask him/her to compute
15400	the factorial of n-1.  Wait for an answer.  When it arrives, multiply it
15450	by n (note that this requires you to remember the value of n) and
15500	then give this answer to the person who originally asked you to
15550	compute the factorial of n.  Then go play.
15600	.SK 1
15650	.END
15700	We shall draw a few stages in the computation of factorial(3).
15750	.FIG 5
15800	PERSON3 is shown giving the problem "factorial(0)" to
15850	PERSON4.  Note that PERSONs 1, 2 and 3 are "remembering" their
15900	values of n while awaiting answers.  Now PERSON4, by step 2,
15950	returns an answer of "1" to PERSON3.  PERSON3 computes
16000	n*1 = 1*1 = 1, and gives that answer to PERSON2, who computes
16050	n*1 = 2*1 = 2 and gives that answer to PERSON1, who
16100	computes n*2 = 3*2 = 6, and gives that answer to PERSON0
16150	(Tom Sawyer).
16200	
16250	Let us now write an ALGOL W ↓_procedure_↓ that mimics the
16300	functions of PERSON1 above:
16350	.ASIS
16400	
16450	INTEGER PROCEDURE PERSON1 (INTEGER VALUE N);
16500	BEGIN INTEGER ANSWER;
16550	COMMENT PERSON1 is "called" in order to compute the factorial of N.
16600		He allocates a variable ANSWER to hold his answer.;
16650	IF N=0 THEN ANSWER := 1
16700	COMMENT The above test implements step 2 of the instructions
16750		outlined above.  However, PERSON1 just records the answer. Later,
16800		he/she will pass it back to the person who called PERSON1.;
16850	ELSE ANSWER := N * PERSON2(N-1) ;
16900	COMMENT This step computes the value of N-1, and calls upon PERSON2
16950		to compute the answer to factorial(n-1).  When that answer is
17000		computed and returned by PERSON2 (PERSON2 will be an
17050		integer procedure), then PERSON1's answer is computed by 
17100		multiplying by N.;
17150	ANSWER
17200	COMMENT Now return the ANSWER to the person who asked for it
17250		(i.e. who called PERSON1).;
17300	END;
17350	
17400	.END
17450	We can shorten the procedure by removing the comments
17500	and using a conditional expression to compute the answer:
17550	.ASIS
17600	
17650	INTEGER PROCEDURE PERSON1 (INTEGER VALUE N);
17700	   IF N=0 THEN 1 ELSE N*PERSON2(N-1);
17750	
17800	.END
17850	Now, of course, we must write a procedure for PERSON2.  The rules are
17900	precisely the same as for PERSON1, so we have:
17950	.ASIS
18000	
18050	INTEGER PROCEDURE PERSON2 (INTEGER VALUE N);
18100	   IF N=0 THEN 1 ELSE N*PERSON3(N-1);
18150	
18200	.END
18250	We could go on and on writing such procedures.  However,
18300	we notice that all the procedures are identical except that they call
18350	upon different PERSONs to solve the simpler problems.  ALGOL W
18400	permits us to define only one PERSON, and ALGOL W
18450	will copy the definition if a new PERSON is required.  Let us name
18500	this person FACTORIAL:
18600	.ASIS
18650	
18700	INTEGER PROCEDURE FACTORIAL (INTEGER VALUE N);
18750	   IF N=0 THEN 1 ELSE N*FACTORIAL(N-1);
18800	
18825	.;GARBAGE45
18850	.END
18900	The use of FACTORIAL(N-1) (second line) in evaluating FACTORIAL(n)
18950	will cause creation of a new copy of the rules for
19000	factorial (i.e. will create a new person) in order to compute
19050	the value of FACTORIAL(N-1).  When each copy returns
19100	its answer, the copy is automatically destroyed.
19150	Thus our drawing of stick figures now turns into a drawing of prcedure
19200	copies, each with the same rules, but a different value of N:
19250	.;THIS3875
19300	.ASIS
19350	
19400	FACTORIAL(3)
19450	IF 3=0 THEN 1 ELSE 3*FACTORIAL(2)
19500	
19550		FACTORIAL(2)
19600		IF 2=0 THEN 1 ELSE 2*FACTORIAL(1)
19650	
19700			FACTORIAL(1)
19750			IF 1=0 THEN 1 ELSE 1*FACTORIAL(0)
19800	
19850				FACTORIAL(0)
19900				IF 0=0 THEN 1 ELSE 0*...
19950	
20000	
20050	
20100	
20150	.END
20200	The dotted lines show the values returned by each copy of
20250	FACTORIAL.
20300	We will now demonstrate the sequence of steps actually
20350	performed by the computer.  Let us label the minute steps of the
20400	FACTORIAL procedure as follows:
20450	.BEGIN INDENT 6,2
20500	.SK 1
20550	F.1#Test to see if N is zero. If true, go to step F.2, otherwise to step F.3
20600	
20650	F.2#Return the answer "1" to the procedure that called us, and
20700	destroy this copy of FACTORIAL.
20750	
20800	F.3#Compute the value of N-1.
20850	
20900	F.4#Create a new copy of the rules for FACTORIAL.  Initialize it so
20950	that its value of N contains the expression computed in step
21000	F.3.  Remember that the next step we must execute when the copy returns
21050	an answer is step F.5.  Now go perform step F.1
21100	of the new copy, and proceed.
21150	
21200	F.5#We come to this step when an answer has been returned
21250	by a copy of FACTORIAL.  Multiply the answer by N.
21300	
21350	F.6#Return this new expression to the procedure that called
21400	us and destroy this copy of FACTORIAL.
21450	.SK 1
21500	.END
21550	If, in the main program, we issued a command 
21600	.ASIS
21650	
21700		I := FACTORIAL (3)
21750	
21800	.END
21850	ALGOL W creates a copy of FACTORIAL with N=3, and starts at step
21900	F.1 of the copy:
21950	.ASIS
22000	
22050	F.1 Is 3=0? No, execute step F.3 next.
22100	F.3 3-1 = 2
22150	F.4 Create a new copy of FACTORIAL with N=2; our next step will
22200	    be F.5 when an answer is returned. Now go to step F.1 of the copy.
22250	   F.1 Is 2=0? No, execute step F.3 next.
22300	   F.3 2-1 = 1
22350	   F.4 Create copy with N=1; our next step is F.5; go to copy.
22400	      F.1 Is 1=0? No, execute step F.3 next.
22450	      F.3 1-1 = 0
22500	      F.4 Create copy with N=0; our next step is F.5; go to copy.
22550	         F.1 Is 0=0? Yes, execute step F.2
22600	         F.2 Return "1" to our caller (i.e. let him pick up computing
22650	             where he left off) and destroy this copy of FACTORIAL.
22700	      F.5 answer*n = 1*1 = 1
22750	      F.6 Return 1 to our caller and destroy this copy.
22800	   F.5 answer*n = 1*2 = 2
22850	   F.6 Return 2 to our caller, and destroy this copy.
22900	F.5 answer*n = 2*3 = 6
22950	F.6 Return 6 to our caller, and destroy this copy.  This will cause
23000	    the value of 6 to be returned to the place in the main prograa that
23050	    called FACTORIAL(3), and thus stored in I.
23100	
23150	.END
23200	We can verify that ALGOL W behaves this way with
23250	the following program:
23300	.ASIS
23350	
23400	BEGIN
23450	INTEGER PROCEDURE FACTORIAL (INTEGER VALUE N);
23500	BEGIN INTEGER ANSWER;
23550	WRITE ("COPY CREATED TO COMPUTE FACTORIAL OF",N);
23600	IF N=0 THEN ANSWER:=1 ELSE ANSWER:=N*FACTORIAL(N-1);
23650	WRITE ("ANSWER TO FACTORIAL OF",N,"IS",ANSWER);
23700	ANSWER
23750	END;
23800	
23850	INTFIELDSIZE := 2;
23900	WRITE (FACTORIAL(3),"IS THE ANSWER");
23950	END.
24000	
24050	.END
24100	You may want to try this on the computer.  The output
24150	will look like:
24200	.ASIS
24250	
24300	COPY CREATED TO COMPUTE FACTORIAL OF 3
24350	COPY CREATED TO COMPUTE FACTORIAL OF 2
24400	COPY CREATED TT COMPUTE FACTORIAL OF 1
24450	COPY CREATED TO COMPUTE FACTORIAL OF 0
24500	ANSWER TO FACTORIAL OF 0 IS 1
24550	ANSWER TO FACTORIAL OF 1 IS 1
24600	ANSWER TO FACTORIAL OF 2 IS 2
24650	ANSWER TO FACTORIAL OF 3 IS 6
24700	    6  IS THE ANSWER
24750	
24800	.END
24850	.SK 2
24900	↓_Example 3: Counting Leaves of a Tree_↓
24950	
25000	Suppose that it its your task to count the number of leaves on a
25050	binary tree:
25100	.FIG 5
25150	A binary tree is one that can only branch two ways at each
25200	junction:
25250	.ASIS
25300	.FIG 3
25350	  Binary junction       3 branches          more branches!
25400	.SK 1
25450	.END
25500	Although you can count the number of leaves on the above tree
25550	very easily, if the tree got very much bigger, even
25600	humans would have trouble keeping things straight (Have I counted this
25650	branch already?).  However, the recursive technique is very simple.
25700	Start at the trunk of the tree (sometimes called the "root") and
25750	use the following rules:
25800	.BEGIN INDENT 6,3
25850	.SK 1
25900	1.#If you hold in your hand a "leaf" (#####), then the answer is "1"
25950	(i.e. there is one leaf on the tree).
26000	
26050	2.#Otherwise, you must hold a branch.  Break the branch in two places:
26100	.FIG 4
26150	and find a person willing to follow these same rules.  Give him/her
26200	piece  A and wait for the answer.  Remember it as
26250	ANSWERA.  Then give the person piece B and wait for an answer, remembered
26300	as ANSWERB.  Now you can compute the answer to the original 
26350	question: it is just ANSWERA+ANSWERB.  This follows because
26400	the answer ANSWERA is (we hope) the number of leaves on
26450	piece A, and ANSWERB is the number of leaves on piece B.  Clearly the
26500	total number of leaves on the original branch is just the sum of these
26550	two numbers.
26600	.END
26650	.SK 1
26700	Once again, this formulation uses the recursive paradigm.  We can now
26750	give a skeleton ALGOL W procedure that implements these rules:
26800	.ASIS
26850	
26900	INTEGER PROCEDURE TREECOUNT ( branch );
26950	  IF branch = leaf THEN 1 ELSE
27000	        TREECOUNT( left(branch) )+ TREECOUNT ( right(branch) );
27050	
27100	.END
27150	Of course ALGOL W can't handle branches, leaves, and left and right
27200	branches directly.  Instead we must ?!represent?! the tree in some
27250	form that ALGOL W can manipulate.  We shall demonstrate two
27300	representations, one using arrays and one using records and
27350	references.
27400	
27450	Suppose that each branch is given a unique integer number.  Then
27500	we set up two integer arrays LEFTBRANCH and RIGHTBRANCH.  For
27550	the tree:
27600	.FIG 6
27650	we have
27700	.ASIS
27750	
27800	LEFTBRANCH(1) = 3		RIGHTBRANCH(1) = 2
27850	LEFTBRANCH(2) = 0		RIGHTBRANCH(2) = 0
27900	LEFTBRANCH(3) = 4		RIGHTBRAHCH(3) = 5
27950	LEFTBRANCH(4) = 0		RIGHTBRANCH(4) = 0
28000	LEFTBRANCH(5) = 0		RIGHTBRANCH(5) = 0
28050	
28100	.END
28150	This representation says that branch 1 divides into branches 3
28200	(LEFTBRANCH(1)) and 2 (RIGHTBRANCH(1)).  However, branch 4 does not
28250	divide (LEFTBRANCH(4) = 0, RIGHTBRANCH(4) = 0) and is therefore
28300	a leaf.
28350	
28400	This representation 
28450	allows us to write the TREECOUNT procedure as follows:
28500	.ASIS
28550	
28600	INTEGER ARRAY LEFTBRANCH,RIGHTBRANCH (1::20);
28650	
28700	INTEGER PROCEDURE TREECOUNT (INTEGER VALUE BRANCH);
28750	   IF LEFTBRANCH(BRANCH)=0 THEN 1 ELSE
28800	      TREECOUNT(LEFTBRANCH(BRANCH))+TREECOUNT(RIGHTBRANCH(BRANCH));
28850	
28900	COMMENT Setup arrays LEFTBRANCH and RIGHTBRANCH here;
28950	
29000	WRITE ("NUMBER OF LEAVES IS",TREECOUNT(1));
29050	
29100	.END
29150	A representation using records and references might be as
29200	follows: we set up a record named TWIG that has two references
29250	to other such records: LEFT and RIGHT.
29300	.ASIS
29350	
29400	RECORD TWIG ( REFERENCE (TWIG) LEFT,RIGHT );
29450	REFERENCE (TWIG) TRUNK;
29500	
29550	INTEGER PROCEDURE TREECOUNT (REFERENCE(TWIG) BRANCH);
29600	   IF LEFT(BRANCH)=NULL THEN 1 ELSE
29650	      TREECOUNT(LEFT(BRANCH))+TREECOUNT(RIGHT(BRANCH));
29700	
29750	COMMENT Setup records to represent the tree here. Assume that
29800		TRUNK is a reference to the twig that represents the trunk.;
29850	
29900	WRITE ("NUMBER OF LEAVES IS",TREECOUNT(TRUNK));
29950	
30000	.END
30050	You may wish to hand compute the answer using the following record
30100	structure (same tree as used in the array example above):
30150	.ASIS
30200	
30250	TRUNK ---->    LEFT  ------->    LEFT  ------->    LEFT  NULL
30300	               RIGHT             RIGHT             RIGHT NULL
30350	
30400	                  LEFT  NULL             LEFT  NULL
30450	                  RIGHT NULL             RIGHT NULL
30500	
30550	.END
30600	This example is the first in which the recursive algorithm is actually
30650	easier to formulate than an iterative form (If you don't believe this,
30700	try to write a non-recursive version of the treecount procedure with
30750	records and references used to represent the tree structure).
30800	
30850	↓_Example 4: Counting Miles_↓
30900	
30950	The design of recursive procedures is not always as easy as in the examples
31000	above.  We have to be particularly careful to avoid "infinite recursion"
31050	just as we have to be careful to avoid "infinite looping" in commands
31100	like:
31150	.ASIS
31200	
31250		WHILE 2<3 DO WRITE ("LOOP");
31300	
31350	.END
31400	Infinite recursion occurs when we are not adequately careful in
31450	formulating the "simpler problem."  For example, if solving problem A
31500	requires solving simpler problem A', which in turn requires solving
31550	"simpler" problem A, we are in trouble!  The following example illustrates
31600	this danger.
31650	
31700	Suppose we have a road map represented by an array of zeroes and ones:
31750	.ASIS
31800	.INDENT 20,20
31850	
31900	10100000000
31950	10100000000
32000	11110001000
32050	00100001000
32100	00111001010
32150	00001111010
32200	01000001010
32250	11110000110
32300	
32350	.END
32400	We are to start in our car at the upper left-hand corner of the map
32450	and follow roads (represented by 1's) to find out how many miles of raod
32500	can be reached from the upper left-hand corner (each 1 represents a
32550	mile of road).  If there is a road at one location, then we must check
32600	to see if it extends to the top, bottom, left or right of the square.
32650	In other words, the squares marked "a" are accessible from that marked
32700	"x":
32750	.ASIS
32800	.INDENT 25,25
32850	
32900	 a
32950	axa
33000	 a
33050	
33100	.END
33150	Let us number rows of the matrix ROAD from i=1 to 8 (top to
33200	bottom) and columns from j=1 to 11 (left to right).
33250	
33300	We can formulate an answer to the problem as follows:
33350	suppose we write a procedure FOLLOW that takes two arguments,
33400	row number i and column number j.  FOLLOW is to return the number
33450	of miles of road that can be reached from position (i,j).
33500	The answer to the problem will then be simply:
33550	.ASIS
33600	
33650	WRITE ("NUMBER OF MILES IS",FOLLOW(1,1));
33700	
33750	.END
33800	What are the commands that FOLLOW must contain? Clearly if ROAD(i,j)=0,
33850	then the answer is zero: there is no road in this square.
33900	Otherwise, the answer can be obtained by adding 1 (for the square
33950	we are on) to the results of FOLLOWing road in the four directions
34000	that can be accessed from our square (i,j):
34050	.ASIS
34100	
34150	1+FOLLOW(I-1,J)+FOLLOW(I+1,J)+FOLLOW(I,J-1)+FOLLOW(I,J+1)
34200	
34250	.END
34300	But we notice one "bug" right away: evaluating FOLLOW(1,1)
34350	will require evaluating
34400	.ASIS
34450	.INDENT 10,10
34500	
34550	FOLLOW(0,1)
34600	FOLLOW(2,1)
34650	FOLLOW(1,0)
34700	FOLLOW(1,2)
34750	
34800	.END
34850	but if i or j are zero we have gone off the road map!  We can fix this
34900	problem by contriving to answer that FOLLOWing any road off the map
34950	yields a route length of zero.  Now we have:
35000	.ASIS
35050	
35100	INTEGER ARRAY ROAD(1::8,1::11);
35150	
35200	INTEGER PROCEDURE FOLLOW (INTEGER VALUE I,J);
35250	BEGIN INTEGER ANSWER;
35300	   IF I=0 OR I=9 OR J=0 OR J=12 THEN ANSWER := 0 ELSE
35350	   IF ROAD(I,J)=0 THEN ANSWER := 0 ELSE
35400	   ANSWER := 1+FOLLOW(I-1,J)+FOLLOW(I+1,J)+FOLLOW(I,J-1)+FOLLOW(I,J+1);
35450	ANSWER
35500	END;
35550	
35600	.END
35650	But alas, this procedure will never return an answer to
35700	FOLLOW(1,1)!  We have generated a program that will recur infinitely.
35750	Luckily, there is a time limit on your program's runtime that will
35800	expire before you consume hours of computer time.
35850	
35900	To see why the program doesn't work properly, we shall "hand simulate"
35950	the FOLLOW procedure using the road map shown above.  We shall draw
36000	the computation with a diagram: a procedure call FOLLOW(i,j)
36050	will be indicated by i and j inside parentheses.
36100	Thus (1,1) represents a call FOLLOW(1,1).
36150	Since ROAD(1,1)=1, the first two IF commands of the FOLLOW procedure
36200	do not pertain, and we must evaluate FOLLOW(0,1), FOLLOW(2,1),
36250	FOLLOW(1,0) and FOLLOW(1,2) in order to compute an answer.
36300	This is indicated diagramatically as follows:
36350	.ASIS
36400	
36450	                 (1,1)
36500	
36550	      (0,1)   (2,1)   (1,0)   (1,2)
36600	
36650	.END
36700	Now we shall underline (___) those cases that return zero, either
36750	because i or j is off the map or because ROAD(i,j)=0:
36800	.ASIS
36850	
36900	                 (1,1)
36950	
37000	      ↓_(0,1)_↓   (2,1)   ↓_(1,0)_↓   ↓_(1,2)_↓
37050	
37100	.END
37150	Now, in computing (2,1), we request four more FOLLOW computations:
37200	.ASIS
37250	
37300	                 (1,1)
37350	
37400	      ↓_(0,1)_↓   (2,1)   ↓_(1,0)_↓   ↓_(1,2)_↓
37450	
37500	      (1,1)   ↓_(3,1)_↓   ↓_(2,0)_↓   ↓_(2,2)_↓
37550	
37600	
37650	.END
37700	This little exercise has uncovered the problem!  In order to evaluate
37750	(1,1), we need to evaluate (1,1).  The trouble is that when (2,1)
37800	tries to explore neighboring squares, it returns to (1,1) which has
37850	already been explored.
37900	
37950	One way to fix this problem is to "erase road" as we explore.
38000	This will prevent exploration of already-explored road.
38050	FOLLOW becomes:
38100	.ASIS
38150	
38200	INTEGER PROCEDURE FOLLOW (INTEGER VALUE I,J);
38250	BEGIN INTEGER ANSWER;
38300	   IF I=0 OR I=9 OR J=0 OR J=12 THEN ANSWER := 0 ELSE
38350	   IF ROAD(I,J)=0 THEN ANSWER := 0 ELSE
38400	   BEGIN
38450	   COMMENT First erase the road under us so that any subsequent
38500	           explorations of this square will answer zero.;
38550	      ROAD(I,J) := 0;
38600	      ANSWER := 1+FOLLOW(I-1,J)+FOLLOW(I+1,J)+
38650	                  FOLLOW(I,J-1)+FOLLOW(I,J+1)
38700	   END;
38750	ANSWER
38800	END;
38850	
38900	.END
38950	Now, since FOLLOW(1,1) sets ROAD(1,1) to zero, our diagram becomes:
39000	.ASIS
39050	
39100	                 (1,1)
39150	
39200	      ↓_(0,1)_↓   (2,1)   ↓_(1,0)_↓   ↓_(1,2)_↓
39250	
39300	      ↓_(1,1)_↓   (3,1)   ↓_(2,0)_↓   ↓_(2,2)_↓
39350	
39400	      ↓_(2,1)_↓   ↓_(4,1)_↓   ↓_(3,0)_↓   (3,2)
39450	
39500	
39550	.END
39600	Notice that we have now underlined the second attempt to explore
39650	(1,1); since we set ROAD(1,1) to zero at the first attempt, the
39700	second attempt will now safely return zero, and will not attempt
39750	to explore all routes leading out of square (1,1) etc.
39800	
39850	↓_Example 5: Finding a Route_↓
39900	
39950	Example 4 actually suggests a way for finding a routine from one spot
40000	on our map to another.  We notice from the branching diagram that the
40050	branches seem to follow along (1,1), (2,1), (3,1), (3,2) ... which
40100	is in fact a sequence of steps along the road.  All we need to do is
40150	provide a mechanism for (a) deciding when we have reached the destination
40200	we seek and (b) then printing out the correct route.
40250	
40300	We can accomplish (a) by comparing i and j to two global variables
40350	IDESTINATION and JDESTINATION.  If both are equal, we have reached
40400	the destination.  We shall change FOLLOW to be a LOGICAL procedure, and
40450	it will return TRUE if there is a route to the destination.  We shall
40500	print out the route as we return through the recursive procedure
40550	calls:
40600	.ASIS
40650	
40700	INTEGER IDESTINATION,JDESTINATION;
40750	INTEGER ARRAY ROAD (1::8,1::12);
40800	
40850	LOGICAL PROCEDURE FOLLOW (INTEGER VALUE I,J);
40900	BEGIN LOGICAL ANSWER;
40950	   IF I=0 OR I=9 OR J=0 OR J=12 THEN ANSWER := FALSE ELSE
41000	   IF ROAD(I,J)=0 THEN ANSWER := FALSE ELSE
41050	      BEGIN
41100	      IF I=IDESTINATION AND J=JDESTINATION THEN
41150	         BEGIN
41200	         WRITE ("(",I,",",J,")");
41250	         ANSWER := TRUE;
41300	         END ELSE BEGIN
41350	         ROAD(I,J) := 0;
41400	         COMMENT First search above;
41450	         ANSWER := FOLLOW(I-1,J);
41500	         COMMENT If no route that way then search below;
41550	         IF ¬ANSWER THEN ANSWER := FOLLOW(I+1,J);
41600	         COMMENT If still no route then search to the left;
41650	         IF ¬ANSWER THEN ANSWER := FOLLOW(I,J-1);
41700	         COMMENT If still no route then search to the right;
41750	         IF ¬ANSWER THEN ANSWER := FOLLOW(I,J+1);
41800	         COMMENT If any of the paths succeeded, then this spot (i,j)
41850	                 is on the successful route! Print it out.;
41900	         IF ANSWER THEN WRITE ("(",I,",",J,")");
41950	         END
42000	      END;
42050	ANSWER
42100	END;
42150	
42200	COMMENT Set up the array ROAD here;
42250	IDESTINATION := 4; JDESTINATION := 8;
42300	
42350	COMMENT Now call FOLLOW.  If it returns FALSE, there was no route.;
42400	IF ¬FOLLOW(1,1) THEN WRITE ("YOU CAN'T GET THERE FROM HERE");
42450	
42500	.END
42550	If we use the road map given above, the route will be printed
42600	out (in reverse) as follows:
42650	.ASIS
42700	.INDENT 10,10
42750	
42800	(4,8)
42850	(5,8)
42900	(6,8)
42950	(6,7)
43000	(6,6)
43050	(6,5)
43100	(5,5)
43150	(5,4)
43200	(5,3)
43250	(4,3)
43300	(3,3)
43350	(3,2)
43400	(3,1)
43450	(2,1)
43500	(1,1)
43550	
43600	.END
43650	This procedure illustrates a ↓_searching_↓ technique.
43700	The philosophy of resursive search is as follows:
43750	.BEGIN INDENT 6,3
43800	.BEGIN INDENT 6,3
43850	.SK 1
43900	1.#Check to see if we are at the goal location.  If so, return
43950	TRUE.
44000	
44050	2.#Otherwise, try to solve one of several simpler search problems by
44100	taking a small motion in one of the available directions and applying
44150	the rules recursively.
44200	.END
44250	.SK 1
44300	We must of course be sure that the searches don't loop.
44350	In the FOLLOW example above, we actually took a slightly different
44400	approach than the search paradigm above: step 2 was divided into two
44450	parts (2a) try all potentially legal paths from this location and
44500	(2b) verify that a potential path is legal (on the map and ROAD(i,j)
44550	non-zero).  Then we wrote the procedure as follows:
44600	.BEGIN INDENT 6,3
44650	.SK 1
44700	2b:#If this (i,j) proposed path is not legal, return FALSE.
44750	
44800	1.#If we are at the goal, return TRUE.
44850	
44900	2a.#Try each potential path from this location.  If ↓_any_↓
44950	of the trials returns TRUE, we have found a path.  In that case,
45000	print out (i,j) since it is on the path, and return TRUE.
45050	If none of the trials returns TRUE, then we must return FALSE.
45100	.END
45150	.SK 2
45200	↓_Concluding Remarks_↓
45250	
45300	Recursion is a very powerful programming technique as well as a way of 
45350	formullting many problems, whether for human or computer solution.
45400	The examples we have given have only scratched the surface of the
45450	technique.
45500	
45550	Many people berate recursion because it is inefficient: all that
45600	"copying" of procedures!  In fact, most programming languages that
45650	permit recursion arrange to copy only a very small amount of information
45700	each time a procedure is called.  Nevertheless, in ALGOL W, the 
45750	recursive method of computing the factorial is substantially more
45800	inefficient (slower) than the iterative method.
45850	An iterativeform of factorial is probably just as easy to understand
45900	as a recursive form.  However, for problems like Examples 3, 4 and 5,
45950	the recursive formulation is substantially simpler than formulations
46000	not using recursion (try it).  Thus we achieve a certain
46050	"programmer efficiency"; and in these cases the non-recursive solutions
46100	require more ALGOL W commands than the recursive formulations, and
46150	the recursive from may not be any slower than the non-recursive
46200	form.
46250	
46300	Different programming languages take different attitudes about
46350	recursion.  FORTRAN, for example, does not permit it.
46400	(The language does not copy procedures when they are called.  This
46450	prevents recursion from working properly.  Why?  Consider what would
46500	happen if only one "copy" of FACTORIAL were available.)
46550	Languages such as ALGOL W, PL/I and CHIRON all permit recursion,
46600	but the cost of recursion is higher than that of, say, iteration.
46650	The LISP language is structured to actively encourage recursion;
46700	in fact recursive formulations are often clearer and more efficient
46750	than iterative ones.
46800	
46850	Many programmers who use recursion frequently start
46900	to "think recursively" when formulating computer programs or
46950	algorithms.  Some of the most powerful and impressive computer
47000	programs (programs that play chess, that "understand" English
47050	sentences, or that compile languages such as ALGOL W into
47100	machine-language) are based on recursive algorithms.
47150	We close with the light-hearted remark attributed to
47200	Peter Deutsch, a virtuoso programmer,
47250	
47300	"To iterate is human, to recurse divine."
47350	.NEXT PAGE
47400	
47450	
47500	↓_Exercises_↓
47550	
47600	1. Write a recursive procedure that will have the same effect as the
47650	ALGOL W skeleton
47700	.ASIS
47750	
47800	FOR I := LOWER UNTIL UPPER DO
47850	     command
47900	
47950	.END
48000	LOWER and UPPER are integer variables, and "command" is some ALGOL W command.
48050	
48100	2. Formulate a solution to Example 3, records and references representation,
48150	that uses no procedures (i.e. a non-recursive solution).  Be careful
48200	to try your program on a variity of trees; also state the conditions
48250	under which your program will not get a correct answer.
48300	
48350	3. What if the tree (Example 3) isn't binary?  Formulate
48400	a solution in which a twig may have 0, 1, 2, or 3 branches leaving it.
48450	
48500	4. Modify FOLLOW (Example 4) so that it does not permanently
48550	destroy the information in the ROAD array.  Be careful that the
48600	modified procedure will not recur infinitely.  (Hint: you need to
48650	add only one ALGOL W command to FOLLOW to solve this problem.)
48700	
48750	5. Arrange to print out the route (Example 5) in the correct orcer.
48800	You might also plot a "map" of the route.
48850	
48900	6. The program of example 5 will not always find the shortest
48950	route from starting point to  the goal.
49000	Construct a road map for which this is the case.  Modify FOLLOW so that
49050	it will find the optimal (shortest) route.
49100	
49150	7. ↓_Blob counting._↓  Suppose we haae an array representation of an image
49200	of (say) blood cells.  We wish to count the number of separate "blobs"
49250	in the image and to measure their sizes.  The rules for blobs are as 
49300	follows: if a square "x" is in a blob, so may be those marked "a":
49350	.ASIS
49400	.INDENT 20,20
49450	
49500	aaa
49550	axa
49600	aaa
49650	
49700	.END
49750	The size of a blob is just the number of squares in it.  For example,
49800	.ASIS
49850	.INDENT 15,15
49900	
49950	00110010
50000	01111010
50050	11110011
50100	11100111
50150	01000110
50200	00011010
50250	
50300	.END
50350	has two blobs of 1's: one is of size 14, one of size 12.
50400	Arrange your program to read in (from data cards) the
50450	dimensions of the image area and the values of the elements
50500	of the array.
50550	
50600	8. The technique of setting ROAD(i,j) to zero to prevent
50650	infinite recursion doesn't work when the problem is represented
50700	with records and references.  Consider trying to search from START
50750	to GOAL in the following structure:
50800	.FIG 15
50850	Design a procedure that will perform the search correctly and that
50900	will leave the structure intact when it is finished.
50950	
51000	9. (After solving problem 8)  ↓_Telephone Line Connections_↓
51050	A telephone network might look as follows:
51100	.FIG 10
51150	The circles represent switching offices, and the number represent
51200	the capacity (in simultaneous conversations) of each connection.
51250	The telephone company has discovered that the "best" path is
51300	one that minimizes the value of
51350	.ASIS
51400	
51450	           N +     50/capacity_of_link
51500	
51550	.END
51600	where N is the number of intermediate switching offices on the path,
51650	and the sum is taken over all telephone links on the path.  Find the
51700	optimal path from A to B in the above network.
51750	
51800	.END
51850	.END
51900	.END
51950	.END